home *** CD-ROM | disk | FTP | other *** search
/ IRIX Base Documentation 2002 November / SGI IRIX Base Documentation 2002 November.iso / usr / share / catman / p_man / cat3 / SCSL / dggsvd.z / dggsvd
Encoding:
Text File  |  2002-10-03  |  10.3 KB  |  331 lines

  1.  
  2.  
  3.  
  4. DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))                                                          DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))
  5.  
  6.  
  7.  
  8. NNNNAAAAMMMMEEEE
  9.      DGGSVD - compute the generalized singular value decomposition (GSVD) of
  10.      an M-by-N real matrix A and P-by-N real matrix B
  11.  
  12. SSSSYYYYNNNNOOOOPPPPSSSSIIIISSSS
  13.      SUBROUTINE DGGSVD( JOBU, JOBV, JOBQ, M, N, P, K, L, A, LDA, B, LDB,
  14.                         ALPHA, BETA, U, LDU, V, LDV, Q, LDQ, WORK, IWORK, INFO
  15.                         )
  16.  
  17.          CHARACTER      JOBQ, JOBU, JOBV
  18.  
  19.          INTEGER        INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
  20.  
  21.          INTEGER        IWORK( * )
  22.  
  23.          DOUBLE         PRECISION A( LDA, * ), ALPHA( * ), B( LDB, * ), BETA(
  24.                         * ), Q( LDQ, * ), U( LDU, * ), V( LDV, * ), WORK( * )
  25.  
  26. IIIIMMMMPPPPLLLLEEEEMMMMEEEENNNNTTTTAAAATTTTIIIIOOOONNNN
  27.      These routines are part of the SCSL Scientific Library and can be loaded
  28.      using either the -lscs or the -lscs_mp option.  The -lscs_mp option
  29.      directs the linker to use the multi-processor version of the library.
  30.  
  31.      When linking to SCSL with -lscs or -lscs_mp, the default integer size is
  32.      4 bytes (32 bits). Another version of SCSL is available in which integers
  33.      are 8 bytes (64 bits).  This version allows the user access to larger
  34.      memory sizes and helps when porting legacy Cray codes.  It can be loaded
  35.      by using the -lscs_i8 option or the -lscs_i8_mp option. A program may use
  36.      only one of the two versions; 4-byte integer and 8-byte integer library
  37.      calls cannot be mixed.
  38.  
  39. PPPPUUUURRRRPPPPOOOOSSSSEEEE
  40.      DGGSVD computes the generalized singular value decomposition (GSVD) of an
  41.      M-by-N real matrix A and P-by-N real matrix B:
  42.          U'*A*Q = D1*( 0 R ),    V'*B*Q = D2*( 0 R )
  43.  
  44.      where U, V and Q are orthogonal matrices, and Z' is the transpose of Z.
  45.      Let K+L = the effective numerical rank of the matrix (A',B')', then R is
  46.      a K+L-by-K+L nonsingular upper triangular matrix, D1 and D2 are M-by-
  47.      (K+L) and P-by-(K+L) "diagonal" matrices and of the following structures,
  48.      respectively:
  49.  
  50.      If M-K-L >= 0,
  51.  
  52.                          K  L
  53.             D1 =     K ( I  0 )
  54.                      L ( 0  C )
  55.                  M-K-L ( 0  0 )
  56.  
  57.                        K  L
  58.             D2 =   L ( 0  S )
  59.                  P-L ( 0  0 )
  60.  
  61.  
  62.  
  63.                                                                         PPPPaaaaggggeeee 1111
  64.  
  65.  
  66.  
  67.  
  68.  
  69.  
  70. DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))                                                          DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))
  71.  
  72.  
  73.  
  74.                      N-K-L  K    L
  75.        ( 0 R ) = K (  0   R11  R12 )
  76.                  L (  0    0   R22 )
  77.  
  78.      where
  79.  
  80.        C = diag( ALPHA(K+1), ... , ALPHA(K+L) ),
  81.        S = diag( BETA(K+1),  ... , BETA(K+L) ),
  82.        C**2 + S**2 = I.
  83.  
  84.        R is stored in A(1:K+L,N-K-L+1:N) on exit.
  85.  
  86.      If M-K-L < 0,
  87.  
  88.                        K M-K K+L-M
  89.             D1 =   K ( I  0    0   )
  90.                  M-K ( 0  C    0   )
  91.  
  92.                          K M-K K+L-M
  93.             D2 =   M-K ( 0  S    0  )
  94.                  K+L-M ( 0  0    I  )
  95.                    P-L ( 0  0    0  )
  96.  
  97.                         N-K-L  K   M-K  K+L-M
  98.        ( 0 R ) =     K ( 0    R11  R12  R13  )
  99.                    M-K ( 0     0   R22  R23  )
  100.                  K+L-M ( 0     0    0   R33  )
  101.  
  102.      where
  103.  
  104.        C = diag( ALPHA(K+1), ... , ALPHA(M) ),
  105.        S = diag( BETA(K+1),  ... , BETA(M) ),
  106.        C**2 + S**2 = I.
  107.  
  108.        (R11 R12 R13 ) is stored in A(1:M, N-K-L+1:N), and R33 is stored
  109.        ( 0  R22 R23 )
  110.        in B(M-K+1:L,N+M-K-L+1:N) on exit.
  111.  
  112.      The routine computes C, S, R, and optionally the orthogonal
  113.      transformation matrices U, V and Q.
  114.  
  115.      In particular, if B is an N-by-N nonsingular matrix, then the GSVD of A
  116.      and B implicitly gives the SVD of A*inv(B):
  117.                           A*inv(B) = U*(D1*inv(D2))*V'.
  118.      If ( A',B')' has orthonormal columns, then the GSVD of A and B is also
  119.      equal to the CS decomposition of A and B. Furthermore, the GSVD can be
  120.      used to derive the solution of the eigenvalue problem:
  121.                           A'*A x = lambda* B'*B x.
  122.      In some literature, the GSVD of A and B is presented in the form
  123.                       U'*A*X = ( 0 D1 ),   V'*B*X = ( 0 D2 )
  124.      where U and V are orthogonal and X is nonsingular, D1 and D2 are
  125.      ``diagonal''.  The former GSVD form can be converted to the latter form
  126.  
  127.  
  128.  
  129.                                                                         PPPPaaaaggggeeee 2222
  130.  
  131.  
  132.  
  133.  
  134.  
  135.  
  136. DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))                                                          DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))
  137.  
  138.  
  139.  
  140.      by taking the nonsingular matrix X as
  141.  
  142.                           X = Q*( I   0    )
  143.                                 ( 0 inv(R) ).
  144.  
  145.  
  146. AAAARRRRGGGGUUUUMMMMEEEENNNNTTTTSSSS
  147.      JOBU    (input) CHARACTER*1
  148.              = 'U':  Orthogonal matrix U is computed;
  149.              = 'N':  U is not computed.
  150.  
  151.      JOBV    (input) CHARACTER*1
  152.              = 'V':  Orthogonal matrix V is computed;
  153.              = 'N':  V is not computed.
  154.  
  155.      JOBQ    (input) CHARACTER*1
  156.              = 'Q':  Orthogonal matrix Q is computed;
  157.              = 'N':  Q is not computed.
  158.  
  159.      M       (input) INTEGER
  160.              The number of rows of the matrix A.  M >= 0.
  161.  
  162.      N       (input) INTEGER
  163.              The number of columns of the matrices A and B.  N >= 0.
  164.  
  165.      P       (input) INTEGER
  166.              The number of rows of the matrix B.  P >= 0.
  167.  
  168.      K       (output) INTEGER
  169.              L       (output) INTEGER On exit, K and L specify the dimension
  170.              of the subblocks described in the Purpose section.  K + L =
  171.              effective numerical rank of (A',B')'.
  172.  
  173.      A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
  174.              On entry, the M-by-N matrix A.  On exit, A contains the
  175.              triangular matrix R, or part of R.  See Purpose for details.
  176.  
  177.      LDA     (input) INTEGER
  178.              The leading dimension of the array A. LDA >= max(1,M).
  179.  
  180.      B       (input/output) DOUBLE PRECISION array, dimension (LDB,N)
  181.              On entry, the P-by-N matrix B.  On exit, B contains the
  182.              triangular matrix R if M-K-L < 0.  See Purpose for details.
  183.  
  184.      LDB     (input) INTEGER
  185.              The leading dimension of the array B. LDA >= max(1,P).
  186.  
  187.      ALPHA   (output) DOUBLE PRECISION array, dimension (N)
  188.              BETA    (output) DOUBLE PRECISION array, dimension (N) On exit,
  189.              ALPHA and BETA contain the generalized singular value pairs of A
  190.              and B; ALPHA(1:K) = 1,
  191.              BETA(1:K)  = 0, and if M-K-L >= 0, ALPHA(K+1:K+L) = C,
  192.  
  193.  
  194.  
  195.                                                                         PPPPaaaaggggeeee 3333
  196.  
  197.  
  198.  
  199.  
  200.  
  201.  
  202. DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))                                                          DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))
  203.  
  204.  
  205.  
  206.              BETA(K+1:K+L)  = S, or if M-K-L < 0, ALPHA(K+1:M)=C,
  207.              ALPHA(M+1:K+L)=0
  208.              BETA(K+1:M) =S, BETA(M+1:K+L) =1 and ALPHA(K+L+1:N) = 0
  209.              BETA(K+L+1:N)  = 0
  210.  
  211.      U       (output) DOUBLE PRECISION array, dimension (LDU,M)
  212.              If JOBU = 'U', U contains the M-by-M orthogonal matrix U.  If
  213.              JOBU = 'N', U is not referenced.
  214.  
  215.      LDU     (input) INTEGER
  216.              The leading dimension of the array U. LDU >= max(1,M) if JOBU =
  217.              'U'; LDU >= 1 otherwise.
  218.  
  219.      V       (output) DOUBLE PRECISION array, dimension (LDV,P)
  220.              If JOBV = 'V', V contains the P-by-P orthogonal matrix V.  If
  221.              JOBV = 'N', V is not referenced.
  222.  
  223.      LDV     (input) INTEGER
  224.              The leading dimension of the array V. LDV >= max(1,P) if JOBV =
  225.              'V'; LDV >= 1 otherwise.
  226.  
  227.      Q       (output) DOUBLE PRECISION array, dimension (LDQ,N)
  228.              If JOBQ = 'Q', Q contains the N-by-N orthogonal matrix Q.  If
  229.              JOBQ = 'N', Q is not referenced.
  230.  
  231.      LDQ     (input) INTEGER
  232.              The leading dimension of the array Q. LDQ >= max(1,N) if JOBQ =
  233.              'Q'; LDQ >= 1 otherwise.
  234.  
  235.      WORK    (workspace) DOUBLE PRECISION array,
  236.              dimension (max(3*N,M,P)+N)
  237.  
  238.      IWORK   (workspace/output) INTEGER array, dimension (N)
  239.              On exit, IWORK stores the sorting information. More precisely,
  240.              the following loop will sort ALPHA for I = K+1, min(M,K+L) swap
  241.              ALPHA(I) and ALPHA(IWORK(I)) endfor such that ALPHA(1) >=
  242.              ALPHA(2) >= ... >= ALPHA(N).
  243.  
  244.      INFO    (output) INTEGER
  245.              = 0:  successful exit
  246.              < 0:  if INFO = -i, the i-th argument had an illegal value.
  247.              > 0:  if INFO = 1, the Jacobi-type procedure failed to converge.
  248.              For further details, see subroutine DTGSJA.
  249.  
  250. PPPPAAAARRRRAAAAMMMMEEEETTTTEEEERRRRSSSS
  251.      TOLA    DOUBLE PRECISION
  252.              TOLB    DOUBLE PRECISION TOLA and TOLB are the thresholds to
  253.              determine the effective rank of (A',B')'. Generally, they are set
  254.              to TOLA = MAX(M,N)*norm(A)*MAZHEPS, TOLB =
  255.              MAX(P,N)*norm(B)*MAZHEPS.  The size of TOLA and TOLB may affect
  256.              the size of backward errors of the decomposition.
  257.  
  258.  
  259.  
  260.  
  261.                                                                         PPPPaaaaggggeeee 4444
  262.  
  263.  
  264.  
  265.  
  266.  
  267.  
  268. DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))                                                          DDDDGGGGGGGGSSSSVVVVDDDD((((3333SSSS))))
  269.  
  270.  
  271.  
  272.              Further Details ===============
  273.  
  274.              2-96 Based on modifications by Ming Gu and Huan Ren, Computer
  275.              Science Division, University of California at Berkeley, USA
  276.  
  277. SSSSEEEEEEEE AAAALLLLSSSSOOOO
  278.      INTRO_LAPACK(3S), INTRO_SCSL(3S)
  279.  
  280.      This man page is available only online.
  281.  
  282.  
  283.  
  284.  
  285.  
  286.  
  287.  
  288.  
  289.  
  290.  
  291.  
  292.  
  293.  
  294.  
  295.  
  296.  
  297.  
  298.  
  299.  
  300.  
  301.  
  302.  
  303.  
  304.  
  305.  
  306.  
  307.  
  308.  
  309.  
  310.  
  311.  
  312.  
  313.  
  314.  
  315.  
  316.  
  317.  
  318.  
  319.  
  320.  
  321.  
  322.  
  323.  
  324.  
  325.  
  326.  
  327.                                                                         PPPPaaaaggggeeee 5555
  328.  
  329.  
  330.  
  331.